perm filename GAL.SAI[AL,HE]5 blob sn#554608 filedate 1981-01-01 generic text, type C, neo UTF8
COMMENT ⊗   VALID 00005 PAGES
C REC  PAGE   DESCRIPTION
C00001 00001
C00002 00002	BEGIN "Force Graphics routines for AL"
C00003 00003	! GET, FOVERLAY, NEW_AL_PROG
C00010 00004	! globals, READ_DATA, GRAPH, PLOT_IT
C00020 00005	!	Main control loop
C00033 ENDMK
C⊗;
BEGIN "Force Graphics routines for AL"

REQUIRE "DDHDR.SAI[GRA,HE]" SOURCE_FILE;

DEFINE	CRLF="('15&'12)",
	CR ="'15",
	LF ="'12",
	! = "COMMENT ",
	TIL="STEP 1 UNTIL";

REQUIRE "11UTIL.HDR[11,SYS]" SOURCE_FILE;

EXTERNAL INTEGER _SKIP_;

DEFINE MAP_OFFSET = "'160000";	! Converts virtual addresses to physical ones;
DEFINE SAILID = "'0";		! The location telling what program it is: 2 for us;
DEFINE NOTB10 = "'2";		! The notebox from 11 to the 10 (byte address);
DEFINE NOTB11 = "'40";		! The notebox from 10 to the 11 (byte address);

define ttyset = "'047000400121";

! GET, FOVERLAY, NEW_AL_PROG;

PROCEDURE GET (STRING gfile);
  BEGIN "get file"
  DEFINE block_size = '4000;	! Load in 2K blocks;
  INTEGER ARRAY packed[1:block_size/2]; ! unpacked[1:block_size];
  INTEGER addr,eof,chn,i;

  chn ← getchan;
  OPEN(chn,"DSK",'10,19,0,0,0,eof);
  LOOKUP(chn,gfile,i);
  IF i THEN BEGIN PRINT("Couldn't lookup ",gfile,crlf); RELEASE(chn); RETURN END;

  WORDIN(chn);	! Ignore program starting address;
  WORDIN(chn);	! Ignore DDT starting address;
  addr ← WORDIN(chn);	! Low address of core image;

  packed[1] ← WORDIN(chn);	! First word of core image;
  DO BEGIN
    ARRYIN(chn,packed[2],block_size/2-1);
!   FOR i ← 1 TIL block_size/2 DO
!	BEGIN					! Unpack it;
!	unpacked[2*i-1] ← packed[i] LSH -18;
!	unpacked[2*i] ← packed[i] LAND '777777;
!	END;
    POKEARRAY(addr,block_size/2,packed,TWRJ); ! block_size,unpacked);
    addr ← addr + 2*block_size;
    packed[1] ← WORDIN(chn);	! Make sure EOF gets set if no more;
  END UNTIL eof;

  CLOSE(chn);
  RELEASE(chn);
  END "get file";


BOOLEAN PROCEDURE FOVERLAY (STRING ofile);
  BEGIN "overlay file"
  INTEGER ARRAY data[1:500];
  INTEGER addr,eof,chn,i,size,cksum;

  SIMPLE INTEGER PROCEDURE READ_BYTE;
    BEGIN
    INTEGER b;
    b ← WORDIN(chn);	! Read next byte;
    cksum ← cksum + b;
    RETURN(b)
    END;

  chn ← getchan;
  OPEN(chn,"DSK",'10,19,0,0,0,eof);
  LOOKUP(chn,ofile,i);
  IF i THEN BEGIN RELEASE(chn); RETURN(false) END;

  WHILE TRUE DO
    BEGIN
    DO i ← WORDIN(chn) UNTIL eof ∨ i=1;		! Find next data block;
    IF eof THEN BEGIN RELEASE(chn); RETURN(TRUE) END;
    IF WORDIN(chn) THEN 			! Skip over 0 word;
	BEGIN PRINT("Bad data in file - aborting"&crlf);
		RELEASE(chn); RETURN(FALSE) END;
    cksum ← 1;
    size ← READ_BYTE + (READ_BYTE LSH 8) - 6;	! # bytes of data;
    addr ← READ_BYTE + (READ_BYTE LSH 8);	! address of this block;
    IF size≤0 THEN BEGIN RELEASE(chn); RETURN(TRUE) END;
    ARRYIN(chn,data[1],size);			! Read in the data;
    data[size+1] ← 0;				! In case size is odd;
    size ← (size+1) div 2;			! Block size in words;
    FOR i ← 1 TIL size DO		! Convert data from bytes to words;
      BEGIN
      cksum ← cksum + data[2*i] + data[2*i-1];		! Compute checksum;
      data[i] ← (data[2*i] LSH 8) + data[2*i-1]
      END;
    READ_BYTE;					! Read in the checksum;
    IF cksum LAND '377 THEN 		! Were low 8 bits of checksum zero?;
	BEGIN PRINT("Checksum error - aborting"&crlf);
		RELEASE(chn); RETURN(FALSE) END;
    POKEARRAY(addr,size,data);			! Ship data over to the 11;
    END
  END "overlay file";

STRING alprog,oldppn;

PROCEDURE NEW_AL_PROG;
  BEGIN "load a bin file"
  STRING filnam,name,ext,ppn;
  BOOLEAN success;

  DO BEGIN ! Get a file name;
    PRINT(" file name: ");
    filnam ← INCHWL;
    IF filnam = NULL ∨ _SKIP_ = '175 THEN
      BEGIN
      PRINT(" aborted"&crlf);
      RETURN;
      END;
    name ← ext ← ppn ← NULL;
    WHILE LENGTH(filnam) > 0 ∧ filnam ≠ "." ∧ filnam ≠ "[" DO
      name ← name & LOP(filnam);
    WHILE LENGTH(filnam) > 0 ∧ filnam ≠ "[" DO ext ← ext & LOP(filnam);
    IF EQU(ext,".") THEN ext ← NULL;
    IF filnam = "[" THEN ppn ← filnam;

    success ← FOVERLAY(name&ext&ppn);	! Try just what we were given;
    IF ¬success ∧ ext = NULL ∧ FOVERLAY(name&".BIN"&ppn) THEN
	BEGIN success ← TRUE; ext ← ".BIN" END;	! Try making it a .BIN file;

    IF ¬success ∧ ppn = NULL THEN
      IF FOVERLAY(name&ext&oldppn) THEN	! Try what we were given on old ppn area;
	BEGIN success ← TRUE; ppn ← oldppn END
      ELSE IF ext = NULL ∧ FOVERLAY(name&".BIN"&oldppn) THEN
	BEGIN success←TRUE;ppn←oldppn;ext←".BIN" END;	! Try making it a .BIN file;

    IF ¬success THEN PRINT("Can't find file: ",name,ext,ppn," - Try again."&crlf)

  END UNTIL success;

  alprog ← name & ext & ppn;
  oldppn ← ppn;

  END "load a bin file";

! globals, READ_DATA, GRAPH, PLOT_IT;

DEFINE DSIZE = 900;	! Allow for 30 seconds of force sampling;

PRELOAD_WITH "FX","FY","FZ","MX","MY","MZ","T1","T2","T3","T4","T5","T6";
STRING ARRAY CTLCHR[1:12];
PRELOAD_WITH 1,2,4,'10,'20,'40,'100,'200,'400,'1000,'2000,'4000;
INTEGER ARRAY CTLMASK[1:12];
PRELOAD_WITH "OZ","OZ","OZ","OZ-IN","OZ-IN","OZ-IN",
	     "OZ-IN","OZ-IN","OZ","OZ-IN","OZ-IN","OZ-IN";
STRING ARRAY YLAB[1:12];

INTEGER ID,CTL,NPTS,fixed_scaling,graph_mode;
BOOLEAN ARRAY GOT[1:12];
INTEGER ARRAY RDATA[1:12*DSIZE];
REAL ARRAY DATA[1:12,1:DSIZE];

PROCEDURE READ_DATA;
  BEGIN "read data"
  INTEGER i,j,k,addr,ncpn,offset;

  addr ← PEEK(NOTB10+MAP_OFFSET);	! Get address of buffer;
  id ← PEEK(addr+MAP_OFFSET);		! Get id number;
  ctl ← PEEK(addr+2+MAP_OFFSET);	! Get force bits;
  npts ← PEEK(addr+4+MAP_OFFSET);	! Get number of data points;

  PRINT("Data being gathered"&crlf);
! DETERMINE WHICH DATA WAS COLLECTED;
  NCPN←0;
  FOR I← 1 STEP 1 UNTIL 12 DO
    IF CTL LAND CTLMASK[I] THEN
	BEGIN
	NCPN←NCPN+1;
	GOT[I]←TRUE;
	PRINT("	",CTLCHR[I]," COLLECTED"&CRLF);
	END
    ELSE GOT[I]←FALSE;
  PRINT("*");

! Read in the raw data - left justified;
  PEEKARRAY(addr+6+MAP_OFFSET,ncpn*npts,RDATA,TWLM);

! STORE RAW DATA INTO SEPARATE ARRAYS;
  OFFSET←1;
  FOR I←1 STEP 1 UNTIL 12 DO
    IF GOT[I] THEN
	BEGIN
	K←OFFSET;
	FOR J←1 STEP 1 UNTIL NPTS DO
	    BEGIN
	    IF RDATA[K]=0 THEN DATA[I,J] ← 0 ELSE
		BEGIN	! Convert 11 floating point to 10 integer;
		INTEGER SIGNEXPONENT,FRACTION,NEWNUM; REAL X;
		SIGNEXPONENT←RDATA[K] LAND '777000000000;
		FRACTION← ((RDATA[K] LAND '777777760) LSH -1)+'400000000;
		NEWNUM←SIGNEXPONENT+FRACTION;
		IF NEWNUM<0 THEN NEWNUM←((LNOT NEWNUM) + 1) LOR '400000000000;
		MEMORY[LOCATION(X),INTEGER]←NEWNUM;
		DATA[I,J] ← X;
		END;
	    K←K+NCPN
	    END;
	OFFSET←OFFSET+1;
	END;
  END "read data";

PROCEDURE GRAPH (INTEGER comp, range(87));
  BEGIN "graph"
    INTEGER I;
    REAL DX,DY,MAXV,MINV,x,y,xx,yy;
    STRING COM2;

    SIMPLE PROCEDURE AVECT(REAL x,y);
	BEGIN
	LINE(xx,yy,x,y);
	xx ← x; yy ← y;
	END;

    SIMPLE PROCEDURE AIVECT(REAL x,y);
	BEGIN
	xx ← x; yy ← y;
	END;

    SIMPLE PROCEDURE RVECT(REAL dx,dy);
	AVECT(xx+dx,yy+dy);

    SIMPLE PROCEDURE RIVECT(REAL dx,dy);
	BEGIN
	xx ← xx+dx; yy ← yy+dy;
	END;

    SIMPLE INTEGER PROCEDURE DRAW_AXIS(INTEGER X0,Y0;REAL DX,DY,NUMDIST;
	INTEGER I0,IM; STRING UNITS);
    !  Draws  an axis scale for a graph.  X0,Y0 specify the origin of the
    graph.  DX,DY specify the direction (and scale) of the  axis.   I0,IM
    specify  the  numeric range of the axis labelling.	UNITS is the name
    of the axis.  Returns the distance between minor "tic" marks  on  the
    axis;
	BEGIN
	INTEGER EI,I,DI,DIN,K,XP,YP;
	REAL EX,EY,X,Y;
	REAL DL;
	DL←ABS(DX)+ABS(DY);
	DIN←5;K←1;
	WHILE DIN*DL<NUMDIST DO
	 DIN←DIN*(CASE (K←K+1) MOD 3 OF (2.5,2.0,2.0));
	DI←DIN DIV 5;
	IF ¬UNITS THEN RETURN(DI);
	EX←(-10*DX)/DL;
	EY←(-10*DY)/DL;
	TXTPOS((XP←X0+(IM-I0)*DX)+10,YP←Y0+(IM-I0)*DY,24,40);
	TEXT(UNITS);
	AIVECT(XP,YP);
	EI←I0 MOD DI;
	IF EI≠0 THEN EI←DI-EI;
	X←X0+EI*DX;
	Y←Y0+EI*DY;
	AVECT(X,Y);
	I0←I0+EI;
	FOR I←I0 STEP DI UNTIL IM DO
	  BEGIN
	  IF I MOD DIN =0 THEN
	    BEGIN
	    RVECT(3*EY,3*EX);
	    RIVECT(5*EY+EX,3*EX+EY);
	    IF I < 0 THEN RIVECT(-24,0);
	    K ← LOG(ABS(I) MAX 1)/LOG(10.0) - 1;
	    RIVECT(-24*K,0);
	    TXTPOS(xx,yy,24,40);
	    TEXT(CVS(I));
	    END
	   ELSE RVECT(EY,EX);
	  AIVECT(X←X+DI*DX,Y←Y+DI*DY);
	END;
	RETURN(DI);
    END "DRAW_AXIS";

    DEFINE X0 = -350;	! Graph orgin;
    DEFINE Y0 = -260;
    DEFINE NX = 680;	! Axis lengths;
    DEFINE NY = 650;

    SETFORMAT(1,0);
    IF ¬GOT[comp] THEN
	BEGIN
	PRINT("Data not collected for that component"&CRLF);
	RETURN;
	END;
    DDINIT;
    IF fixed_scaling THEN
       BEGIN
       MINV ← -range;
       MAXV ← range
       END
    ELSE
       BEGIN			    ! Determine the min and max;
       MINV ← MAXV ← data[comp,1];
       FOR I ← 2 STEP 1 UNTIL npts DO
	 IF (y←data[comp,I]) > MAXV THEN MAXV←y
	    ELSE IF y < MINV THEN MINV←y
       END;
    DX ← NX / (npts-1);			! Scale the axes;
    DY ← NY / (MAXV-MINV);
!   DX ← NX DIV (npts-1);		! Scale the axes;
!   DY ← NY DIV (MAXV-MINV);
!   IF DX < 1 THEN DX ← NX/(npts-1);	! May need to rescale so DX,DY ≠ 0;
!   IF DY < 1 THEN DY ← NY/(MAXV-MINV);
    i ← DRAW_AXIS(X0,Y0,DX,0,100,1,npts,"Samples");       ! Draw the axes;
    i ← DRAW_AXIS(X0,Y0,0,DY,40,MINV,MAXV,CTLCHR[comp]&" "&YLAB[comp]);

    IF graph_mode THEN
	BEGIN						! Continuous;
	AIVECT(X0,dy*(data[comp,1]-MINV)+Y0);		! Graph it;
	FOR I ← 2 STEP 1 UNTIL npts DO AVECT(dx*(I-1)+X0,dy*(data[comp,I]-MINV)+Y0);
	END
    ELSE
	BEGIN						! Discrete;
	y ← dy*(data[comp,1]-MINV)+Y0;
	AIVECT(X0-dx/2,y);
	x ← X0+dx/2;
	AVECT(x,y);
	FOR I ← 2 STEP 1 UNTIL npts DO
	  BEGIN
	  y ← dy*(data[comp,I]-MINV)+Y0;
	  AVECT(x,y);
	  x ← X0+dx*(I-0.5);
	  AVECT(x,y);
	  END
	END;

    x ← X0 + dx * (npts -30);	! Show where the arm servo stopped;
    FOR I ← 20 STEP 70 UNTIL NY DO
      BEGIN
      AIVECT(x,Y0+I);
      RVECT(0,10)
      END;

    COM2←"Duration = "&CVS(NPTS/60)&"."&CVS((NPTS MOD 60)/6)&" Seconds";
    TXTPOS(-10-12*LENGTH(COM2),-360,24,40);
    TEXT(COM2);
    PPPOS(-365,-480);
    DPYUP(-1);
      quick_code
      hrroi 1,['004000000120]; comment [004000,,"P"];
      ttyset 1,     ;		    ! this last stuff does an esc-P;
      end;
  END "graph";

PROCEDURE PLOT_IT;
  BEGIN "plot"	! SAVE PLT FILE IF REQUESTED;
    STRING FILNAM;
    PRINT("lot title: ");
    FILNAM ← INCHWL;
    TXTPOS(-10-12*LENGTH(FILNAM),-400,24,40);
    TEXT(FILNAM);
    DPYUP(-1);
    PRINT("Plot file name: ");
      quick_code
      hrroi 1,['004000000120]; comment [004000,,"P"];
      ttyset 1,     ;		    ! this last stuff does an esc-P;
      end;
    FILNAM←INCHWL;
    IF FILNAM = NULL ∨ _SKIP_ = '175 THEN
	BEGIN
	PRINT(" aborted"&crlf);
	RETURN;
	END;
    PUTDDF(FILNAM &".PLT");	! Save plot file;
  END "plot";

!	Main control loop;

INTEGER i,j,k,command,dum,dat11,auto_continue,freeze11,idle;
REAL scale_factor;
STRING ANS,DISCM;
PRELOAD_WITH CVSIX("DSK"),CVSIX("11TTY"),CVSIX("DMP"),0,CVSIX("  1  3"),0;
SAFE INTEGER ARRAY RUN[1:6];	! This is used to swap to 11TTY;

PRINT(crlf&"AL Force Data Gathering Module"&crlf&crlf&crlf);

! Set up our default operating modes;

auto_continue ← FALSE;
fixed_scaling ← FALSE;
graph_mode ← TRUE;	! Continuous;
freeze11 ← TRUE;
alprog ← NULL;
oldppn ← "[f,arg]";
dat11 ← FALSE;
idle ← 0;
scale_factor ← 1;

alinit;				! Grab the elf;
POKE(SAILID+MAP_OFFSET,2);	! Tell AL that we're here to talk to it;
SCREEN(-512,-480,512,480);	! Set up screen dimensions for graphics routines;
LITEN;

WHILE true DO
  BEGIN
  PRINT("*");
  WHILE (command←INCHRS)<0 DO
    BEGIN
    IF ¬dat11 ∧ PEEK(NOTB10+MAP_OFFSET) ∧ PEEK(NOTB10+2+MAP_OFFSET) THEN
	 BEGIN		! Buffer present & data valid;
	 READ_DATA;
	 IF auto_continue THEN POKE(NOTB10+MAP_OFFSET,0) ! Clear buffer pointer;
	    ELSE dat11 ← TRUE;
	 IF ¬freeze11 THEN POKE(NOTB10+2+MAP_OFFSET,0); ! Clear valid data flag;
	 idle ← 0;
	 END
	ELSE CALL(0,"SLEEP");	! Sleep for 1 tick;
    idle ← idle + 1;
    IF idle = 20000 THEN PRINT("Are you still there???" & crlf & "*");
    IF idle ≥ 36000 THEN
	BEGIN
	PRINT("Auto-exit!!!" & crlf);
	POKE(SAILID+MAP_OFFSET,0); ! Tell AL that we're no longer here to talk to it;
	CALL(0,"EXIT");
	END;
    END;
  IF "A" ≤ command ≤ "Z" THEN command ← command LOR '40;     ! Make it lower case;
  idle ← 0;

  CASE command OF	! = a,c,d,e,f,g,h,l,m,p,q,r,s,t,w,x,z,?,1,↑,↓;
    BEGIN

["f"] BEGIN "display force"
      i ← (INCHRW LOR '40) - "w";	! Get which force component;
      IF 1 ≤ i ≤ 3 THEN
	BEGIN			! Okay value;
	PRINT(crlf);
	GRAPH(i,87*scale_factor);	! Default range for forces = 87;
	END
      ELSE PRINT("?"&crlf);
      END "display force";

["m"] BEGIN "display moment"
      i ← (INCHRW LOR '40) - "w" + 3;	! Get which moment component;
      IF 4 ≤ i ≤ 6 THEN
	BEGIN			! Okay value;
	PRINT(crlf);
	GRAPH(i,300*scale_factor);	! Default range for moments = 300;
	END
      ELSE PRINT("?"&crlf);
      END "display moment";

["t"] BEGIN "display joint torque"
      i ← (INCHRW LOR '40) - "0" + 6;	! Get which joint torque component;
      IF 7 ≤ i ≤ 12 THEN
	BEGIN			! Okay value;
	PRINT(crlf);
	GRAPH(i,1000*scale_factor);	! Default range for joint torques = 1000;
	END
      ELSE PRINT("?"&crlf);
      END "display joint torque";

["d"] BEGIN "start"
      PRINT("dt started"&crlf);
      STRT11('130000);
      END "start";

["z"] BEGIN "zero"
      PRINT("ero memory [Confirm] ");
      IF (i←INCHRW) = cr ∨ (i LOR '40) = "y" THEN
	FILL(0,'500000/2,0)
       ELSE PRINT(" Aborted"&crlf);
      IF (i LOR '40) = "y" THEN PRINT(crlf) ELSE INCHRS
      END "zero";

["c"] BEGIN "continue"
      PRINT("ontinue"&crlf);
      POKE(NOTB10+MAP_OFFSET,0);	! Clear buffer pointer;
      POKE(NOTB10+2+MAP_OFFSET,0);	! Clear valid data flag;
      dat11 ← FALSE;
      END "continue";

["a"] BEGIN "auto_continue"
      PRINT("uto-continue now ");
      auto_continue ← ¬ auto_continue;	! Toggle auto_continue;
      IF auto_continue THEN PRINT("on"&crlf) ELSE PRINT("off"&crlf);
      IF auto_continue THEN freeze11 ← FALSE; ! Don't stop after each gathering move;
      END "auto_continue";

["w"] BEGIN "wait"
      PRINT("ait after gathering moves now ");
      freeze11 ← ¬ freeze11;		! Toggle waiting;
      IF freeze11 THEN PRINT("on"&crlf) ELSE PRINT("off"&crlf);
      END "wait";

["s"] BEGIN "fixed_scaling"
      PRINT("caling is now ");
      fixed_scaling ← ¬ fixed_scaling;	! Toggle fixed_scaling;
      IF fixed_scaling THEN PRINT("fixed"&crlf) ELSE PRINT("automatic"&crlf);
      END "fixed_scaling";

["↑"] BEGIN "double scaling"
      scale_factor ← 2 * scale_factor;		! Double default scaling;
      SETFORMAT(5,2);
      PRINT(" double scaling - scale factor is now = ",scale_factor,crlf);
      END "double scaling";

["↓"] BEGIN "halve scaling"
      scale_factor ← 0.5 * scale_factor;	! Halve default scaling;
      SETFORMAT(5,2);
      PRINT(" halve scaling - scale factor is now = ",scale_factor,crlf);
      END "halve scaling";

["g"] BEGIN "graph_mode"
      PRINT("raph mode is now ");
      graph_mode ← ¬ graph_mode;	! Toggle graph_mode;
      IF graph_mode THEN PRINT("continuous"&crlf) ELSE PRINT("discrete"&crlf);
      END "graph_mode";

["p"] BEGIN "plot file"
      PLOT_IT;
      END "plot file";

["l"] BEGIN "load new bin file"
      PRINT("oad new AL program"&crlf);
      NEW_AL_PROG;
      STRT11('130000);	! Start up DDT too;
      END "load new bin file";

["r"] BEGIN "reload AL runtime"
      PRINT("eload AL runtime system [Confirm] ");
      IF (i←INCHRW) = cr ∨ (i LOR '40) = "y" THEN
	BEGIN
	IF (i LOR '40) = "y" THEN PRINT(crlf) ELSE INCHRS;
	FILL(0,'500000/2,0);	  ! Zero memory;
	GET("AL.SAV[AL,HE]");
	IF alprog ≠ NULL THEN FOVERLAY(alprog)			! Load the old one;
	  ELSE BEGIN PRINT("AL program"); NEW_AL_PROG; END;	! or get a new one;
	POKE(SAILID+MAP_OFFSET,2);	! Tell AL that we're here to talk to it;
	STRT11('130000);  ! Start up DDT too;
	END
       ELSE PRINT(" Aborted"&crlf);
      END "reload AL runtime";

["x"] BEGIN "reload ALX runtime"
      PRINT("perimental AL runtime system being loaded [Confirm] ");
      IF (i←INCHRW) = cr ∨ (i LOR '40) = "y" THEN
	BEGIN
	IF (i LOR '40) = "y" THEN PRINT(crlf) ELSE INCHRS;
	FILL(0,'500000/2,0);	  ! Zero memory;
	GET("ALX.SAV[AL,HE]");
	IF alprog ≠ NULL THEN FOVERLAY(alprog)			! Load the old one;
	  ELSE BEGIN PRINT("AL program"); NEW_AL_PROG; END;	! or get a new one;
	POKE(SAILID+MAP_OFFSET,2);	! Tell AL that we're here to talk to it;
	STRT11('130000);  ! Start up DDT too;
	END
       ELSE PRINT(" Aborted"&crlf);
      END "reload ALX runtime";

["1"] BEGIN "11TTY"
      PRINT("1TTY being swapped in [Confirm] ");
      IF (i←INCHRW) = cr ∨ (i LOR '40) = "y" THEN
	BEGIN
	PRINT(crlf&crlf);
	POKE(SAILID+MAP_OFFSET,0); ! Tell AL that we're no longer here to talk to it;
	CALL('1000000+LOCATION(RUN[1]),"RUN")
	END
       ELSE PRINT(" Aborted"&crlf);
      END "11TTY";

["e"] BEGIN "exit"
      PRINT("xit"&crlf);
      POKE(SAILID+MAP_OFFSET,0); ! Tell AL that we're no longer here to talk to it;
      DONE;
      END "exit";

["q"] BEGIN "quit"
      PRINT("uit"&crlf);
      POKE(SAILID+MAP_OFFSET,0); ! Tell AL that we're no longer here to talk to it;
      DONE;
      END "quit";

["?"]
["h"] BEGIN "help"
      IF command = "h" THEN PRINT("elp"&crlf);
	quick_code
	hrroi 1,['004000000516]; comment [004000,,'400+"N"];
	ttyset 1,     ;		      ! this last stuff does a brk-N;
	end;
      PRINT("Commands are:
	FX, FY, FZ - display force data along specified axis
	MX, MY, MZ - display torque data about specified axis
	T1, T2, T3, T4, T5, T6 - display torque data about specified joint
	Graph mode select - toggles between continuous or discrete
	Scaling for force axis of graphs - toggles between fixed & automatic
	Plot, produces plot file for xgp (via PLOT) - asks for file name
	Continue with next gathering move
	Wait after each gathering move - toggled   (cleared by Auto-continue)
	Auto-continue, if on AL won't stop between gathering moves - toggled
	DDT started
	Zero 11's memory
	Reload AL runtime system (or X for experimental AL system)
	Load new AL program - asks for file name
	11TTY should be loaded and run
	Exit or Quit
	Help or ? for this text
	 if a command asks for Confirmation type a ""y"""&crlf);
      END "help";

[cr]  BEGIN "crlf"
      IF INCHRS< 0 THEN PRINT("?"&crlf);	! Gobble the line feed;
      END "crlf";

[lf]  BEGIN "lf"		! Ignore the line feed;
      PRINT(cr&'0);
      END "lf";

ELSE  PRINT("?"&crlf)

    END
  END;

  quick_code
  hrroi 1,['004000000516]; comment [004000,,'400+"N"];
  ttyset 1,	;		! this last stuff does a brk-N;
  end;
  CALL(0,"EXIT");

END